home *** CD-ROM | disk | FTP | other *** search
- .MODEL MEMMOD,C
- LOCALS
- %MACS
- .LALL
- extrn ctick:proc
-
- ; Hardware vector for timer linkage
- ; We use the timer hardware channel here instead of the indirect BIOS
- ; channel (1ch) because the latter is sluggish when running under DoubleDos
- TIMEVEC EQU 08h
-
- .DATA
- public Intstk,Stktop,Spsave,Sssave
- extrn Isat:byte
- Spsave dw ? ; Save location for SP during interrupts
- Sssave dw ? ; Save location for SS during interrupts
- Intstk dw 512 dup(?) ; Interrupt working stack
- Stktop equ $ ; SP set here when entering interrupt
- mtasker db ? ; Type of higher multitasker, if any
-
- .CODE
- dbase dw @Data
- jtable dw l0,l1,l2,l3,l4,l5,l6,l7,l8,l9,l10,l11,l12,l13,l14,l15
-
- ; common routine for interrupt return
- public doret
- label doret far
- cmp Isat,1
- jnz @@1 ; Only one 8259, so skip this stuff
- mov al,0bh ; read in-service register from
- out 0a0h,al ; secondary 8259
- nop ; settling delay
- nop
- nop
- in al,0a0h ; get it
- or al,al ; Any bits set?
- jz @@1 ; nope, not a secondary interrupt
- mov al,20h ; Get EOI instruction
- out 0a0h,al ; Secondary 8259 (PC/AT only)
- @@1: mov al,20h ; 8259 end-of-interrupt command
- out 20h,al ; Primary 8259
- pop es
- pop di
- pop si
- pop bp
- pop dx
- pop cx
- pop bx
- pop ax
- mov ss,Sssave
- mov sp,Spsave ; restore original stack context
- pop ds
- iret
-
- ; Null interrupt handler
- public nullvec
- nullvec proc
- iret
- nullvec endp
-
- ; istate - return current interrupt state
- public istate
- istate proc
- pushf
- pop ax
- and ax,200h
- jnz @@1
- ret
- @@1: mov ax,1
- ret
- istate endp
-
- ; dirps - disable interrupts and return previous state: 0 = disabled,
- ; 1 = enabled
- public dirps
- dirps proc
- pushf ; save state on stack
- cli ; interrupts off
- pop ax ; original flags -> ax
- and ax,200h ; 1<<9 is IF bit
- jnz @@1 ; nonzero -> interrupts were on
- ret
- @@1: mov ax,1
- ret
- dirps endp
-
- ; restore - restore interrupt state: 0 = off, nonzero = on
- public restore
- restore proc
- arg is:word
- test is,0ffffh
- jz @@1
- sti
- ret
- @@1: cli
- ret
- restore endp
-
- ; multitasker types
- NONE equ 0
- DOUBLEDOS equ 1
- DESQVIEW equ 2
-
- ; Relinquish processor so other task can run
- public giveup
- giveup proc
- pushf ;save caller's interrupt state
- sti ;re-enable interrupts
- cmp mtasker, DOUBLEDOS
- jnz @@1
- mov al,2 ; 110 ms
- mov ah,0eeh
- int 21h
- popf ; restore interrupts
- ret
-
- @@1: cmp mtasker, DESQVIEW
- jnz @@2
- mov ax, 1000h
- int 15h
- popf ; restore interrupts
- ret
-
- @@2: hlt ; wait for an interrupt
- popf ; restore interrupts
- ret
- giveup endp
-
- ; check for a multitasker running
- public chktasker
- chktasker proc
- mov mtasker,NONE
- ; do the doubledos test
- mov ah,0e4h
- int 21h
- cmp al,1
- jz @@1
- cmp al,2
- jnz @@2
- @@1: mov mtasker, DOUBLEDOS
- ret
-
- ; test for desqview
- @@2: mov ax, 2b01h
- mov cx, 4445h
- mov dx, 5351h
- int 21h
- cmp al, 0ffh
- jnz @@3
- ret
-
- @@3: mov mtasker, DESQVIEW
- ret
- chktasker endp
-
- ; getss - Read SS for debugging purposes
- public getss
- getss proc
- mov ax,ss
- ret
- getss endp
-
- ; Internet checksum subroutine
- ; Compute 1's-complement sum of data buffer
- ; Uses an unwound loop inspired by "Duff's Device" for performance
- ;
- ; Called from C as
- ; unsigned short
- ; lcsum(buf,cnt)
- ; unsigned short *buf;
- ; unsigned short cnt;
- public lcsum
- lcsum proc
- arg buf:ptr,cnt:word
-
- if @Datasize NE 0
- uses ds,si
- lds si,buf ; ds:si = buf
- else
- uses si
- mov si,buf ; ds:si = buf (ds already set)
- endif
-
- mov cx,cnt ; cx = cnt
- cld ; autoincrement si
- mov ax,cx
- shr cx,1 ; cx /= 16, number of loop iterations
- shr cx,1
- shr cx,1
- shr cx,1
-
- inc cx ; make fencepost adjustment for 1st pass
- and ax,15 ; ax = number of words modulo 16
- shl ax,1 ; *=2 for word table index
- lea bx,jtable ; bx -> branch table
- add bx,ax ; index into jump table
- clc ; initialize carry = 0
- mov dx,0 ; clear accumulated sum
- jmp word ptr cs:[bx] ; jump into loop
-
- ; Here the real work gets done. The numeric labels on the lodsw instructions
- ; are the targets for the indirect jump we just made.
- ;
- ; Each label corresponds to a possible remainder of (count / 16), while
- ; the number of times around the loop is determined by the quotient.
- ;
- ; The loop iteration count in cx has been incremented by one to adjust for
- ; the first pass.
- ;
- deloop: lodsw
- adc dx,ax
- l15: lodsw
- adc dx,ax
- l14: lodsw
- adc dx,ax
- l13: lodsw
- adc dx,ax
- l12: lodsw
- adc dx,ax
- l11: lodsw
- adc dx,ax
- l10: lodsw
- adc dx,ax
- l9: lodsw
- adc dx,ax
- l8: lodsw
- adc dx,ax
- l7: lodsw
- adc dx,ax
- l6: lodsw
- adc dx,ax
- l5: lodsw
- adc dx,ax
- l4: lodsw
- adc dx,ax
- l3: lodsw
- adc dx,ax
- l2: lodsw
- adc dx,ax
- l1: lodsw
- adc dx,ax
- l0: loop deloop ; :-)
-
- adc dx,0 ; get last carries
- adc dx,0
- mov ax,dx ; result into ax
- xchg al,ah ; byte swap result (8088 is little-endian)
- ret
- lcsum endp
-
- ; Link timer handler into timer chain
- ; Arg == address of timer handler routine
- ; MUST be called exactly once before uchtimer is called!
-
- toff dw ? ; save location for old vector
- tseg dw ? ; must be in code segment
-
- public chtimer
- chtimer proc
- arg vec:far ptr
- uses ds
-
- mov ah,35h ; get current vector
- mov al,TIMEVEC
- int 21h ; puts vector in es:bx
- mov cs:tseg,es ; stash
- mov cs:toff,bx
-
- mov ah,25h
- mov al,TIMEVEC
- lds dx,vec ; ds:si = vec
-
- int 21h ; set new vector
- ret
- chtimer endp
-
- ; unchain timer handler from timer chain
- ; MUST NOT be called before chtimer!
- public uchtimer
- uchtimer proc
- uses ds
-
- mov ah,25h
- mov al,TIMEVEC
- mov dx,toff
- mov ds,tseg
- int 21h ; restore old vector
- ret
- uchtimer endp
-
- ; Clock tick interrupt handler. Note the use of "label" rather than "proc"
- ; here, necessitated by the fact that "proc" automatically generates BP-saving
- ; code that we don't want here.
-
- public btick
- label btick far
-
- pushf
- push ds
- cli
- mov ds,cs:dbase ; establish interrupt data segment
-
- mov Sssave,ss ; stash user stack context
- mov Spsave,sp
-
- mov ss,cs:dbase
- lea sp,Stktop
-
- push ax ; save user regs on interrupt stack
- push bx
- push cx
- push dx
- push bp
- push si
- push di
- push es
-
- call ctick
-
- pop es
- pop di
- pop si
- pop bp
- pop dx
- pop cx
- pop bx
- pop ax
- mov ss,Sssave
- mov sp,Spsave ; restore original stack context
- pop ds
- popf
- jmp dword ptr [toff] ; link to previous vector
-
- ; Convert 32-bit int in network order to host order (dh, dl, ah, al)
- ; Called from C as
- ; int32 get32(char *cp);
-
- public get32
- get32 proc
- arg cp:ptr
- if @Datasize NE 0
- uses ds,si
- lds si,cp ; ds:si = cp
- else
- uses si
- mov si,cp ; ds:si = cp (ds already set)
- endif
-
- cld
- lodsw
- mov dh,al ; high word to dx, a-swapping as we go
- mov dl,ah
- lodsw
- xchg al,ah ; low word stays in ax, just swap
- ret
- get32 endp
-
- ; Convert 16-bit int in network order to host order (ah, al)
- ; Called from C as
- ; int16 get16(char *cp);
-
- public get16
- get16 proc
- arg cp:ptr
- if @Datasize NE 0
- uses ds,si
- lds si,cp ; ds:si = cp
- else
- uses si
- mov si,cp ; ds:si = cp (ds already set)
- endif
-
- cld
- lodsw
- xchg al,ah ; low word stays in ax, just swap
- ret
- get16 endp
-
- ; Convert 32-bit int to network order, returning new pointer
- ; Called from C as
- ; char *put32(char *cp,int32 x);
-
- public put32
- put32 proc
- arg cp:ptr,x:dword
- if @Datasize NE 0
- uses ds,di,si
- les di,cp ; es:di = cp
- mov ax,ss ; our parameter is on the stack, and ds might not
- mov ds,ax ; be pointing to ss.
- else
- uses di,si
- mov di,cp ; es:di = cp
- mov ax,ds ; point es at data segment
- mov es,ax
- endif
-
- cld
- lea si,x ; point si to input doubleword
- lodsw ; fetch low word of machine version
- mov dh,al ; swap bytes and save
- mov dl,ah
- lodsw ; fetch high word
- xchg ah,al ; byte swap
- stosw ; store in output
- mov ax,dx ; retrieve low word and store in output
- stosw
- mov ax,di ; return incremented output pointer
- if @Datasize NE 0
- mov dx,es ; upper half of pointer
- endif
- ret
- put32 endp
-
- ; Convert 16-bit int to network order, returning new pointer
- ; Called from C as
- ; char *put16(char *cp,int16 x);
-
- public put16
- put16 proc
- arg cp:ptr,x:word
- uses di,si
- if @Datasize NE 0
- les di,cp ;es:di = cp
- else
- mov di,cp ; es:di = cp
- mov ax,ds
- mov es,ax
- endif
- cld
- mov ax,x ; fetch source word in machine order
- xchg ah,al ; swap bytes
- stosw ; save in network order
- mov ax,di ; return new output pointer to user
- if @Datasize NE 0
- mov dx,es ; upper half of pointer
- endif
- ret
- put16 endp
-
- ; kbraw - raw, nonblocking read from console
- ; If character is ready, return it; if not, return -1
- public kbraw
- kbraw proc
- mov ah,06h ; Direct Console I/O
- mov dl,0ffh ; Read from keyboard
- int 21h ; Call DOS
- jz @@1 ; zero flag set -> no character ready
- mov ah,0 ; valid char is 0-255
- ret
- @@1: mov ax,-1 ; no char, return -1
- ret
- kbraw endp
-
- end
-